home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Gold Medal Software 3
/
Gold Medal Software - Volume 3 (Gold Medal) (1994).iso
/
graphics
/
3dvect30.arj
/
3D2.ASM
< prev
next >
Wrap
Assembly Source File
|
1993-11-18
|
24KB
|
817 lines
;3d vector routines full sorting method (slower)
;
; - objects can pass through one another and still be sorted correctly
; - maxsurfs and maxpoints must be large - set to TOTAL points/surfs on screen
;
; to use:
;
; call look_at_it ; make camera look at selected object
; call setsincose ; set rotation multipliers for eye
; call show_stars ; plot background stars
; call makeobjs ; plot all objects in sides table
; call instant_mouse ; plot mouse on screen
; call flip_page ; flip video pages
; call clear_fill ; clear video memory (last screen)
; call resetupd ; reset update for borders
; call updvectors ; move objects around, rotate them
.386p
jumps
code32 segment para public use32
assume cs:code32, ds:code32
; define externals
extrn objbase:dword ; object lists and bitmap lists are
extrn bitbase:dword ; external! set to 0 if none
extrn bitx:dword ; x and y sizes for 3d conversion
extrn bity:dword
include pmode.inc ; protected mode externals
include xmouse.inc ; xmode mouse externals
include xmode.inc ; xmode externals by matt pritchard
include irq.inc
include font.inc
include macros.inc
include equ.inc
include vars2.inc ; labels and such
align 16
include arctan.inc ; inverse tan
include sin.inc ; sin/cosin table
include shading.inc ; arctan shading tables
include math.inc ; rotate, cos,sin,arctan...
include xscale.inc
include poly.inc ; common ploygon stuff
public makeobjs
public make1obj
public flush_surfaces
public init_tables
strip_bytes equ 4
align 16
abort_all:
add esp,strip_bytes ; abort from loadpoints and make1obj
ret ; returning now from makeobjs call
align 16
loadpoints:
mov bl,userotate[esi]
mov si,whatshape[esi*2] ; get shape, bp = z distance
mov esi,objbase[esi*4]
sub esi,4
view_is_not_ok:
add esi,4
lodsd
cmp eax,zad ; check if too far to see detail anyway
jb s view_is_not_ok
lodsd
add esi,eax
llkk:
mov ax,[esi]
mov numpoints,ax
movzx edi,pointindex ; set xp,yp,zp pointer
add ax,1 ; compensate for center of gravity point
shl ax,1
add ax,pointindex ; pointindex = word indexer to last point
cmp ax,maxpoints*2 ; test for overflow in points tables
jae abort_all
mov ax,[esi+2]
mov numsides,ax
add ax,showing
cmp ax,maxsurfaces-1 ; check for overflow in "sides" tables
jae abort_all
add esi,4+50 ; skip point and side totals, skip future data
mov lindex,di ; set last index to points (this one)
add di,2 ; compensate for center of gravity point
middle_load_points:
or bl,bl ; check userotate command
jne s np13 ; use different loop if no rotation
np12:
mov bx,[esi] ; x
mov cx,[esi+2] ; y
mov bp,[esi+4] ; z
push edi esi
call rotate ; rotate based on object matrix
add ebp,zad
cmp ebp,ztruncate
jge s ntrunct
neg ebp
cmp ebp,ztruncate
jge s ntrunct
mov ebp,ztruncate
ntrunct:
add ebx,xad
add ecx,yad
call make3d
pop esi edi
mov xp[edi],bx
mov yp[edi],cx
mov zp[edi],bp
add di,2 ; inc xp indexer
add esi,6 ; inc input pointer
dec numpoints
jne s np12
mov pointindex,di ; save for next call of loadpoints
ret ; esi exits with pointer to sides
np13:
mov bx,[esi] ; x
mov cx,[esi+2] ; y
mov bp,[esi+4] ; z
push edi esi
call rotatenull ; rotation matrix already set up! (camera)
add ebp,zad
cmp ebp,ztruncate
jge s ntrunct2
neg ebp
cmp ebp,ztruncate
jge s ntrunct
mov ebp,ztruncate
ntrunct2:
add ebx,xad
add ecx,yad
call make3d
pop esi edi
mov xp[edi],bx
mov yp[edi],cx
mov zp[edi],bp
add di,2 ; inc xp indexer
add esi,6
dec numpoints
jne s np13
mov pointindex,di ; save for next call of loadpoints
ret
align 16
; handle loading of bitmap from object list
; eg dw 32,8,5,50,60 ;command is 32,point 8, bitmap 5, x&y scaling of 50,60
ld_special:
lodsw ; get from si, first is point
shl ax,1
add ax,lindex ; add to include offset in list
stosw ; put in sides table
mov dx,bp ; save indexer
movzx ebp,ax ; get point indexers
mov ax,zp[ebp]
mov zeds[ebx],ax ; set zed for sort.
mov bp,dx
movsw ; get bitmap type
movsw ; get x then y scaling
movsw
mov dx,command ; get command (for iteration bits)
mov textures[ebx],dx
cmp zad,64000 ; bitmaps farther than 65536 screw up
jge no_norml ; you can't see them anyway. prevent overflow
jmp ln3
align 16
loadsides:
mov edi,offsides ; get ready for lodsw and stosw
mov ebp,edi ; ebp = offset to first point in side
movzx ebx,showing ; bx = word indexer for surfaces
shl bx,1
ld_lp:
lodsw ; get command word
mov command,ax
test ax,himap ; if bitmap, do special load,
jnz ld_special ; or test previous color
lodsd ; get texture data/type
mov texture12,eax
lodsd ; get colour, high byte is other side
mov colors12,eax
mov cx,lindex ; quick add for loop
lodsw ; get from si, first is unconditinal
shl ax,1
add ax,cx ; add to include offset in list
stosw ; put in di
mov dx,ax
ld_loop:
lodsw ; get from si
shl ax,1
add ax,cx
stosw ; put in di
cmp ax,dx ; check all after first point
je s ld_exitloop
lodsw ; get from si
shl ax,1
add ax,cx
stosw ; put in di
cmp ax,dx ; check all after first point
je s ld_exitloop
lodsw ; get from si
shl ax,1
add ax,cx
stosw ; put in di
cmp ax,dx ; check all after first point
jne s ld_loop
ld_exitloop:
push ebp
push esi
push ebx
mov edi,ebp ; adjust bp into appropriate indexer
movzx ebp,w [edi+2]
mov cx,[zp+ebp]
mov bp,dx ; get point indexers
add cx,[zp+ebp] ; take average of two z points for sort
mov zeds[ebx],cx
mov dx,command
test dx,onscr ; find if test is for on screen pixels
jnz test_if_on_screen
test dl,both+point+line ; check if always visible
jnz its_line
return_screen:
mov bx,[edi+4]
mov dx,[xp+ebp] ; first point
mov ax,[yp+ebp]
mov esq,ax ; memory
mov bp,[edi+2]
mov si,[xp+ebp] ; second point
mov ax,[yp+ebp]
mov dsq,ax ; memory
mov bp,bx
mov di,[xp+ebp] ; third point
mov bp,[yp+ebp]
call checkfront ; check if side is visable using p1,2,3
pop ebx
pop esi ; return object data pointer
pop ebp ; return where we are in sides list
mov dx,command
or ecx,ecx
jle s test_shading ; cx>-1 if side visible, skip if not
test dx,double ; test to use other colour
jz s skipit ; miss this side...
shr texture12,16
shr colors12,16
xor w texture12,inverse ; do inverse shading xor dx,256
test_shading:
test texture12,shade+last
jnz handle_shading ; shading bit set, do it...
ln2:
test dx,check ; find out if side is only a test side
jnz s no_show
mov ax,w texture12 ; another side added...
mov textures[ebx],ax
mov ax,w colors12
mov surfcolors[ebx],ax
ln3:
inc showing ; another side added...
add bx,2
add ebp,maxpolys*2 ; bump ebp to next block
no_show:
test dx,iterate ; test dx,512
jnz handle_surface_iteration
skipit:
test dx,normal ; do we skip surface normal data
jz s no_norml
add esi,6
no_norml:
test dx,iterate ; test dx,512
jnz failed_iteration ; skip iteration data if surface failure
return_iteration:
mov edi,ebp ; set di for next stosw
dec numsides ; count for next side
jne ld_lp
mov offsides,edi ; save for next call
ret
align 16
its_line:
pop ebx esi ebp
test w texture12,shade+last
jz s ln2
; handle gourad/lambert shading
align 16
handle_shading:
test w texture12,last ; test to use previous colour or bitmap call
jnz ld_do_previous
if usesteel eq yes
test w texture12,wavey
jnz ln2
endif
push ebx esi ebp dx
cmp lamflag,no ; is lambert matrix set up?
je s setitup ; jump to less likely route
return:
lodsw ; get surface normal
movsx ebx,ax
lodsw
movsx ecx,ax
lodsw
movsx ebp,ax
call lrotate ; rotate surface normal by lambert matrix
pop dx
test w texture12,inverse ; have the sides flipped? test dx,256
jnz s invert_colour ; jump to least likely route
lp_contin:
add edi,256
shr di,1 ; result -256 to +256, turn into 0-256
mov al,b shading_tables[edi] ; now into 0-15
xor ah,ah
pop ebp esi ebx
add w colors12,ax ; user can have offset color in object!
jmp ln2
align 16
invert_colour: ; inversion occures with other side option,
neg edi ; always visible option, and shading option
jmp lp_contin ; all combined!
align 16
setitup:
push esi
mov esi,currobj ; this is object # from make1obj
call lambert ; set up lambert maxtrix
mov lamflag,yes
pop esi
jmp s return
align 16
ld_do_previous:
mov ax,w colors12
mov cx,surfcolors[ebx-2]
and cx,00fh ; drop old colour block, keep shading indexer
add cx,ax ; add new colour block
mov w colors12,cx
jmp ln2
; handle option 512
align 16
handle_surface_iteration:
test dx,normal
jz s no_norml2
add esi,6 ; skip if shading normal present
no_norml2:
lodsw ; get number of extra points in iteration
mov numpoints,ax ; set as counter
mov cx,ax ; save number of extra points for later use
shl ax,1
add ax,pointindex ; pointindex = word indexer to last point
cmp ax,maxpoints*2 ; test for overflow in points tables
jae abort_all2
lodsw ; get number of sides in iteration
add numsides,ax
add ax,showing
cmp ax,maxsurfaces-1 ; check for overflow in "sides" tables
jae abort_all2
add esi,25*2
or cx,cx ; no new points to add? (just surfaces)
je return_iteration
push ebx ebp dx ; save load and store locations
mov edi,currobj ; add more points to xp,yp,zp list
mov bl,userotate[edi] ; because iteration is visible
mov di,pointindex ; movzx edi,pointindex
call middle_load_points
pop dx ebp ebx
jmp return_iteration
align 16
abort_all2:
add esp,strip_bytes ; abort from iteration and make1obj
ret ; returning now from makeobjs call
; perform test for option 1024 - generate iteration if points on screen.
; routine also tests if polygon crosses screen - eg no point is on the screen
; but the polygon covers the screen, like the front of a very big building.
align 16
test_if_on_screen:
xor bl,bl ; bl = quadrant flag
push dx ; save command
mov esi,ebp
tios:
mov cx,xp[esi] ; cx, dx =(x,y) to test
mov dx,yp[esi]
mov ah,32 ; 32 16 8 determine where point is,
cmp cx,xmins ;1 x x x then or bl with location
jl s ytest ;2 x x x
mov ah,8 ;4 x x x
cmp cx,xmaxs ;
jge s ytest
mov ah,16
ytest:
mov al,1
cmp dx,ymins
jl s oritall
mov al,4
cmp dx,ymaxs
jge s oritall
cmp ah,16
je s on_screen ; a point is on the screen, generate side...
oritall:
or bl,ah ; point is not on the screen, but it may
or bl,al ; contribute to a polygon which covers the screen.
add edi,2 ; get next connection for another test
mov si,sides[edi]
cmp si,bp ; test if at last connection in iteration test
jne tios
xor al,al ; count number of bits in y (must be >2)
ror bl,1
adc al,0
ror bl,1
adc al,0
ror bl,1
adc al,0
cmp al,1
jbe s skipit2
xor al,al ; now count x (must be >2)
ror bl,1
adc al,0
ror bl,1
adc al,0
ror bl,1
adc al,0
cmp al,1
jbe s skipit2
on_screen:
pop dx
test dx,both ; side is on screen
jz return_screen ; test if alway visible
pop ebx esi ebp ; always, pop and test for shading
test dx,shade
jz ln2 ; no shading - do normal return
jmp handle_shading
skipit2:
pop dx ebx esi ebp
jmp skipit
; handle failure of option 512
align 16
failed_iteration:
add esi,4 ; skip # of points and # of surfaces
xor ecx,ecx
lodsw ; number of bytes to skip in case of failure
mov cx,ax
lodsw ; get number of points TOTAL in iteration
shl ax,1 ; in case iteration in iteration in iteration...
add pointindex,ax
add esi,ecx
jmp return_iteration
align 16
; make object esi, routine assumes object is already ON! note: esi not si!
make1obj:
mov lamflag,no
mov currobj,esi
shl si,2 ; si = dword
mov ebx,xs[esi] ; displacement
sub ebx,eyex
mov ecx,ys[esi]
sub ecx,eyey
mov ebp,zs[esi]
sub ebp,eyez
shr ebx,8 ; account for decimal places
test ebx,00800000h
jz s pm_1
or ebx, 0ff000000h
pm_1:
shr ecx,8
test ecx,00800000h
jz s pm_2
or ecx, 0ff000000h
pm_2:
shr ebp,8
test ebp,00800000h
jz s pm_3
or ebp, 0ff000000h
pm_3:
cmp ebx,-maxz ; check if within visible space
jl s noa2 ; if object miles away, don't bother
cmp ebx,maxz
jg s noa2
cmp ebp,-maxz
jl s noa2
cmp ebp,maxz
jg s noa2
cmp ecx,-maxz
jl s noa2
cmp ecx,maxz
jng s mo_misout
align 4
noa2:
ret
mo_misout:
call zsolve ; figure out camera displacement
cmp esi,minz ; check if behind camera, miminum dist.
jl s noa2
call xsolve
mov xad,edi ; store 3d offsets
call make3dx ; now make object farther in 3d
cmp edi,xmit ; tolerance is max object size/ratio
jl s noa2
cmp edi,xmat
jge s noa2
call ysolve ; solve y and set correct regs
mov yad,ecx
call make3dy ; now make object farther in 3d
cmp ecx,ymit
jl s noa2
cmp ecx,ymat
jge s noa2
mov zad,ebp
movzx esi,pointindex
mov xp[esi],bx ; save center of gravity as point 0
mov yp[esi],cx
mov zp[esi],bp
mov esi,currobj ; pop original object number
mov al,userotate[esi]
test al,himap+point ; check if bitmap or point
jnz s mo_special
mov ebx,palxref[esi*4]
mov palxref,ebx
test al,1+himap+point ; test to call compound routine
jnz s mk_skipc ; skip if anything other than full rotations
call compound ; full rotation object, calc. matrix
mk_skipc:
call loadpoints ; load points and rotate, exit di=sides
jmp loadsides ; now load sides, starting at di
align 16
noa:
ret
align 16
; if userotate = 32 then draw bitmap at location x,y,z
mo_special:
cmp pointindex,(maxpoints-1)*2 ; check if there is room in table
jge s noa
cmp showing,maxsurfaces-1
jge s noa
test userotate[esi],point ; is point or bitmap?
jnz mo_ispoint
cmp ecx,ymit ; test if bitmap visible
jl s noa
cmp ecx,ymat
jge s noa
cmp ebp,65535 ; far bitmaps screw up, abort
jge s noa
movzx edi,pointindex
mov [xp+edi],bx ; set location of bitmap
mov [yp+edi],cx
mov [zp+edi],bp
mov edi,offsides
add offsides,maxpolys*2 ; update for next object/bitmap
movzx ebx,showing
shl bp,1 ; adjust so it's the same as loadsides
mov zeds[ebx*2],bp ; set z sort indexer
inc showing ; one more surface...
xor ah,ah
mov al,userotate[esi]
mov textures[ebx*2],ax ; set command for bitmap
mov ax,pointindex
add pointindex,2
stosw
mov ax,whatshape[esi*2]
stosw
mov ax,vxs[esi*2] ; set x and y scales (stretching)
stosw
mov ax,vys[esi*2]
stosw
noa4:
ret
align 16
mo_ispoint:
cmp bx,xmins ; draw single point/bullet
jl s noa4
cmp bx,xmaxs
jge s noa4
cmp cx,ymins
jl s noa4
cmp cx,ymaxs ; ymaxs1 if larger pixel
jge s noa4
movzx edi,pointindex
mov [xp+edi],bx ; set location of point/bitmap
mov [yp+edi],cx
mov [zp+edi],bp
mov edi,offsides
add offsides,maxpolys*2 ; update for next object/bitmap
movzx ebx,showing
shl bx,1
mov zeds[ebx],bp ; set z sort indexer
inc showing ; one more surface...
mov textures[ebx],64 ; set this command as point
mov surfcolors[ebx],bulletcolour ; only for variable colours
mov ax,pointindex
add pointindex,2
stosw
stosw
noa8:
ret
align 16
set_order:
movzx ecx,showing
jcxz s non2_do
dec ecx
jz s non2_do
shl ecx,1
mov esi,ecx
add esi,offset order
prc equ 8
cmp cx,prc*2
jb s ordrloop
bigsloop:
i=0
rept prc
mov [esi+i],cx
i=i-2
sub cx,2
endm
jz s non2_do
sub esi,prc*2
cmp cx,prc*2
jae s bigsloop
ordrloop:
mov [esi],cx
sub esi,2
dec cx
loop ordrloop
non2_do:
mov [order],0 ; fill last
ret
align 16
makeobjx: ; make all objects, unrolled loop
i=1
rept maxobjects
local itsoff
test onoff+i,255 ; check on/off
jz s itsoff
mov esi,i
call make1obj
itsoff:
i=i+1
endm
ret ; put no code here! make1obj may force abort!
; initialize stuff before beginning 3d animation
init_tables:
mov offsides, offset sides ; clear table indexers for call
mov pointindex,0
mov showing,0
ret
align 16
makeobjs:
call makeobjx ; make objects
flush_surfaces:
call set_order ; set ordering of sides
call sort_list ; sort sides according to z distance
call drawvect ; draw 'em on da screen
mov offsides, offset sides ; clear table indexers for call
mov pointindex,0
ret
code32 ends
end